home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Libris Britannia 4
/
science library(b).zip
/
science library(b)
/
PROGRAMM
/
COBOL
/
H309.ZIP
/
PSICO.ZIP
/
PSICO12.EXE
/
PSHELP.C74
< prev
next >
Wrap
Text File
|
1993-02-05
|
14KB
|
441 lines
@ACCEPT
ACCEPT identifier [ FROM mnemonic-name ]
Example:
ACCEPT WS-NUMBER FROM CONSOLE
@ADMIT
The PSICO ADMIT body is part of the POSIT structure. It can only be
entered by a QUIT statement from the POSIT body, or from another structure
nested within the POSIT.
See also POSIT and QUIT
@ADD
Format 1:
ADD numeric-item TO ╠ identifer [ ROUNDED ] ╣
[ [ ON ] SIZE ERROR imperative-statement]
where numeric-item is an identifier or a literal
and all entries between ╠ and ╣ may be repeated
Format 2:
ADD numeric-item ╠ numeric-item ╣ GIVING identifier [ROUNDED]
[ [ ON ] SIZE ERROR imperative-statement]
Format 3:
ADD CORRESPONDING identifer-1 TO identifer-2 [ROUNDED]
[ [ ON ] SIZE ERROR imperative-statement]
Note: CORRESPONDING can be abbreviated to CORR
@ALTER
This is obsolete and will be deleted at the next revision of the ANSI
standard for COBOL
@CALL
CALL item [ USING identifer ╠, identifier ╣ ]
where item is a dataname or a literal program name
and all entries between ╠ and ╣ may be repeated
@CANCEL
CANCEL item
where item is a dataname or a literal program name
@CASE
The PSICO SELECT structure can contain as many CASE clauses as required,
each having its own COBOL condition. The CASE body is only performed if the
stated condition is true.
If the final CASE does not contain a condition, it is treated as an ELSE
case. If you leave the condition field blank, PSICO assumes that this is
the last case.
@CLOSE
CLOSE file-name [, file-name]
@COMPUTE
COMPUTE identifier [ ROUNDED ] = arithmetic-expression
[ [ ON ] SIZE ERROR imperative-statement]
@DELETE
DELETE file-name [ RECORD ]
[ INVALID [ KEY ] imperative-statement]
@DISPLAY
DISPLAY item [ UPON mnemonic-name ]
@DIVIDE
Format 1:
DIVIDE numeric-item INTO identifier [ ROUNDED ]
[ [ ON ] SIZE ERROR imperative-statement]
Format 2:
DIVIDE numeric-item {INTO or BY} numeric-item
GIVING identifier [ ROUNDED ]
[ REMAINDER identifier ]
[ [ ON ] SIZE ERROR imperative-statement]
where numeric-item is an identifier or a literal
@EVALUATE
ANS85 COBOL only
@INITIALIZE
INITIALIZE item ╠, item ╣
[ REPLACING ║ { ALPHANUMERIC } [ DATA ] BY item ] ║
║ { NUMERIC } ║
╠ { ALPHANUMERIC-EDITED } ╣
║ { NUMERIC-EDITED } ║
║ { ALPHABETIC } ║
where all entries between ╠ and ╣ may be repeated
@INSPECT
Format 1:
INSPECT identifier-1 TALLYING
║ identifier-2 ║
║ FOR ║ { { ALL } ║ item ║ { BEFORE } [ INITIAL ] item ║ } ║ ║ ║
║ ║ { { LEADING } ╠ ╠ { AFTER } ╣ } ╣ ║ ║
╠ ╠ { } ╣ ╣
║ ║ { CHARACTERS ║ { BEFORE } [ INITIAL ] item ║ } ║ ║
║ ╠ { AFTER } ╣ ║
Format 2:
INSPECT identifier-1 REPLACING
║ { { ALL } ║ item BY item ║ { BEFORE } [ INITIAL ] item ║ } ║ ║
║ { { LEADING } ╠ ╠ { AFTER } ╣ } ╣ ║
╠ { { FIRST } } ╣
║ ║
║ { CHARACTERS BY item ║ { BEFORE } [ INITIAL ] item ║ } ║
║ ╠ { AFTER } ╣ ║
where all entries between ╠ and ╣ may be repeated
Formats 1 & 2 can be combined into a single statement, with the TALLYING
clause preceding the REPLACING clause
#
Format 3:
INSPECT identifier-1 CONVERTING
item TO item { BEFORE } [ INITIAL ] item }
{ AFTER }
@MENU
The MENU functions available are
E Enter EDIT mode (Mainframe versions only)
F Create a COBOL File definition
L Create a LINKAGE data item.
If LINKAGE SECTION is not present, it will be put in
WORKING-STORAGE
W Create a WORKING-STORAGE item
- View or amend next highr level of nesting
+ View or amend next lower level of nesting
?XXX to obtain help on a COBOL or PSICO command,
eg ?UNSTRING, or ?PROC
@MERGE
Not yet written
@MOVE
Format 1:
MOVE item TO identifier ╠, identifier ╣
where all entries between ╠ and ╣ may be repeated
Format 2:
MOVE CORRESPONDING identifier-1 TO identifier-2
Note: CORRESPONDING can be abbreviated to CORR
@MULTIPLY
Format 1:
MULTIPLY item BY identifier [ ROUNDED ]
[ [ ON ] SIZE ERROR imperative-statement]
Format 2:
MULTIPLY item BY item
GIVING identifier [ ROUNDED ]
[ [ ON ] SIZE ERROR imperative-statement]
@OPEN
OPEN ║ { INPUT } ╠ filename ╣ ║
╠ { OUTPUT } ╣
║ { I-O } ║
║ { EXTEND } ║
where all entries between ╠ and ╣ may be repeated
Example:
OPEN INPUT FILE-1 FILE2
OUTPUT FILE-3
I-O FILE-4
@PERFORM
Format 1:
PERFORM procedure-name-1 [ THRU procedure-name-2 ]
Format 2:
PERFORM procedure-name-1 [ THRU procedure-name-2 ]
numeric-item TIMES
Format 3:
PERFORM procedure-name-1 [ THRU procedure-name-2 ]
UNTIL condition
#
Format 4:
PERFORM procedure-name-1 [ THRU procedure-name-2 ]
VARYING name-1 FROM item BY item UNTIL condition
[ ╠ AFTER VARYING name-2 FROM item BY item UNTIL condition ╣ ]
where all entries between ╠ and ╣ may be repeated
@POSIT
The PSICO POSIT is a type of selection structure in which the condition
does not have to be at the start of the structure.
It is often used to avoid deep nesting of IF-THEN-ELSE statements,
especially in validation.
A QUIT statement anywhere within the POSIT body, or within any structure
nested inside it, transfers control to the associated ADMIT body, which
must exist (but may be empty).
If a label is specified, you may nest POSIT's and then QUIT to the level
which is named. QUIT :OUTER will quit a POSIT labelled OUTER, even from
within other POSIT's nested within it.
See also QUIT and POSIT
@PROCTYPE
A PSICO PROC is equivalent to a COBOL section. This generator and the
associated COBFORM preprocessor provide several types of procedure:
PROC
A normal COBOL procedure. This is the default
IPROC
A JSP Inverted procedure, either single or multi-threading depending
on the PSVNAME and PSVTHREAD specified
RPROC
A recursive procedure, callable from within itself. See also RCALL
@PROCNAME
The procedure name will be used as a COBOL SECTION name, and must therefore
conform to the correct COBOL format.
@PSVNAME
A numeric data item or array to be used for the Progam State Variable in an
Inverted or Recursive procedure.
@PSVTHREAD
A single numeric data item used as a thread index in an Inverted
procedure, or as a Stack Pointer in a recursive routine.
It must NOT contain an OCCURS clause.
@READ
There are two main formats, sequential and random (keyed)
READ filename [ NEXT ] [ RECORD ] [ INTO identifier ]
[ [ AT ] END imperative-statement
READ filename [ INTO identifier ]
[ KEY [ IS ] identifier ]
[ INVALID [ KEY ] imperative-statement ]
See also STATUS
@REWRITE
Rewrite a record which has previously been read. File must be opened I-O
for this to be valid. Can be sequential or keyed.
@QUIT
The PSICO QUIT is a controlled GOTO which allows transfer of control from
the POSIT body to the ADMIT body of a POSIT structure. It is often used to
avoid deep nesting of IF-THEN-ELSE statements, especially in validation.
A QUIT statement anywhere within the POSIT body, or within any structure
nested inside it, transfers control to the associated ADMIT body, which
must exist. Any number of QUIT's may be coded within one POSIT
If a label is specified, you may nest POSIT's and then QUIT to the level
which is named. QUIT :OUTER will quit a POSIT labelled OUTER, even from
within other POSIT's nested within it.
You may also QUIT a labelled iteration (UNTIL, WHILE or TIMES) structure.
In this case, you MUST specify the label, and control is transferred to
the next statement after the end of the iteration.
See also POSIT and ADMIT
@SEARCH
There are two formats for the table handling verb SEARCH. In both formats,
there can be as many WHEN clauses as required
a) SEQUENTIAL search
SEARCH identifier-1 [ VARYING identifier-2 or index-name ]
AT END imperative-statement
║ WHEN condition ║
╠ { imperative-statement } ╣
║ { NEXT SENTENCE } ║
where all entries between ╠ and ╣ may be repeated
If you want to start at the beginning of the table, you must reset the
index to 1. Failure to do this is the most common cause of SEARCH bugs
b) BINARY search. The table MUST be sorted into order
SEARCH ALL identifier-1
AT END imperative-statement
║ WHEN condition ║
╠ { imperative-statement } ╣
║ { NEXT SENTENCE } ║
@SELECT
The PSICO SELECT structure is an extended IF, and can contain as many CASE
clauses as required, each having its own COBOL condition.
Only ONE of the CASE bodies will be performed, the first for which the
condition is found to be true.
If the final CASE does not contain a condition, it is treated as an ELSE
case. If you leave the condition field blank, PSICO assumes that this is
the last case.
@SEQ
A PSICO sequence structure contains a number of COBOL statements and/or
structure commands to be obeyed sequentially.
The sequence body is the only structure in PSICO which can contain more
than 10 lines.
The SEQ command can be used within any other structure to enable extra
lines to be input.
@SEQUENCE
A PSICO sequence structure contains a number of COBOL statements and/or
structure commands to be obeyed sequentially.
The sequence body is the only structure in PSICO which can contain more
than 10 lines.
The SEQ command can be used within any other structure to enable extra
lines to be input.
@START
This positions the file pointer to just before the first record which
fulfils the key condition.
START filename KEY [ NOT ] { = } dataname
{ > }
{ < }
[ INVALID [ KEY ] imperative-statement ]
@STATUS
Some file status values are defined as part of the COBOL definition, but
many implementors have added their own codes to the list.
Major key Minor key
0 Success Some values indicate warnings
1 AT END
2 INVALID KEY 1 = file sequence error (REWRITE, ?WRITE)
2 = duplicate key (WRITE)
3 = record with key does not exist (START, READ)
4 = key out of range (WRITE)
3 File Error 4 = file full,
5 = file not found (OPEN)
9 = file does not match definition
4 Logic Error 1 = File already open (OPEN)
2 = File not open (CLOSE)
3 = REWRITE on record not previously read
4 = record size wrong (WRITE, REWRITE)
6 = read fails, previous read not successful
7,8,9 = file not open in correct mode
@STRING
STRING ║ ╠ item ╣ DELIMITED { SIZE } ║ INTO identifier
╠ { identifier } ╣
║ { literal } ║
[ WITH POINTER numeric-item ]
[ ON OVERFLOW imperative-statement ]
where all entries between ╠ and ╣ may be repeated
@UNSTRING
UNSTRING identifier
[ DELIMITED [ BY ] [ ALL ] item
╠ OR [ ALL ] item ╣ INTO
╠ identifier [ DELIMITER [ IN ] identifier] [ COUNT [ IN ] identifier ] ╣
[ [ WITH ] POINTER numeric-item ]
[ TALLYING [ IN ] numeric-item ]
[ ON OVERFLOW imperative-statement ]
where all entries between ╠ and ╣ may be repeated
@UNTIL
A PSICO UNTIL structure contains a body which will be executed UNTIL the
specified condition is TRUE. The test is at the start, and if the condition
is initially TRUE, the body will not be executed at all.
If you need more than 10 lines in the body, you should use SEQ to create a
sequence structure within the body.
@WHILE
A PSICO WHILE structure contains a body which will be executed WHILE the
specified condition is TRUE. The test is at the start, and if the condition
is initially FALSE, the body will not be executed at all.
If you need more than 10 lines in the body, you should use SEQ to create a
sequence structure within the body.
@TIMES
A PSICO TIMES structure contains a body which will be executed a specified
number of times. The controlling number can be either a literal, or held in
a numeric data item.
If you need more than 10 lines in the body, you should use SEQ to create a
sequence structure within the body.
@ZIF
A PSICO ZIF structure creates a COBOL IF-THEN-ELSE. No other structures
can be nested within these, because of the restrictions of COBOL74.
It is recommended that you use the SELECT statement instead.
@WRITE
Several formats
WRITE record-name
WRITE record-name BEFORE/AFTER ADVANCING
WRITE (keyed)
See also STATUS
@ZREAD
A PSICO ZREAD structure creates a COBOL READ-AT-END. No other structures
can be nested within these, because of the restrictions of COBOL74.